TableReadId Function

private function TableReadId(lines) result(id)

Read the Id of the table. Id is mandatory and must be unique. Arguments: lines collections of lines Result: Return Id

Arguments

Type IntentOptional Attributes Name
character(len=LINELENGTH), intent(in), POINTER :: lines(:)

Return Value character(len=300)


Variables

Type Visibility Attributes Name Initial
character(len=300), public :: before
integer(kind=short), public :: i
logical, public :: idFound
integer(kind=short), public :: ios
character(len=LINELENGTH), public :: string

Source Code

FUNCTION TableReadId &
  ( lines )            &
RESULT (id)

! Module used:
USE StringManipulation, ONLY: &
! imported routines:
StringCompact, StringToUpper, StringSplit

IMPLICIT NONE

! Function arguments
! Scalar arguments with intent(in):
CHARACTER (LEN = LINELENGTH), INTENT (IN), POINTER :: lines (:)

! Local scalars:
CHARACTER (LEN = 300)  :: id 
INTEGER (KIND = short) :: ios
INTEGER (KIND = short) :: i
CHARACTER (LEN = LINELENGTH)  :: string
CHARACTER (LEN = 300)  :: before
LOGICAL                :: idFound            
!------------end of declaration------------------------------------------------

string = ''
idFound = .FALSE.

! scan table 
DO i = 1, SIZE (lines)
  string =  lines (i)
  CALL StringSplit ( ':', string, before)
  
  IF (  StringToUpper ( before(1:2)) == "ID" ) THEN !found id
    CALL StringSplit ( '#', string, before) !remove inline comments
    id = before
    idFound = .TRUE.
    RETURN
  END IF
END DO

IF ( .NOT. idFound ) THEN !Id is mandatory in a table
  CALL Catch ('error', 'TableLib', 'Table Id not found')
END IF
END FUNCTION TableReadId